home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
compilefile.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
4KB
|
164 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% Compile all procedures on a file:
% Uses procedure 'compileclause' from lower level.
% This version uses set and access, which are defined in util.garbcoll
% Set/access codes:
% 1: garbage collect
% 2: compiler options
% 3: temporary variable allocation
% 4: Prolog version
bim :- set(4, bimprolog).
c :- set(4, cprolog).
q :- set(4,quintusprolog).
% Compile 'FileName' and put results in 'Filename.w':
% Default: no special options.
plm(FileName) :- !, plm(FileName, []).
plm(FileName, One) :- atomic(One), \+(One=[]), !, plm(FileName, [One]).
plm(FileName, One) :- \+(list(One)), \+(One=[]), !, plm(FileName, [One]).
plm(FileName, OptionList) :-
q, % Default is Quintus Prolog
access(4, cprolog),
% Handle options:
options(FileName, OptionList),
% Read input file:
see(FileName), read_clauses(CI), seen,
write('Finished reading '), write(FileName),nl,
name(FileName, NL),
name('.w', DOTW),
concat(NL, DOTW, OF),
name(OutFile, OF),
% Compile & write output file:
tell(OutFile),
Start is cputime,
% for dummy procedures
set(dummy_counter,0),
compileallprocs(CI),
Time is cputime-Start,
told,
write('Total cputime is '),write(Time),nl,
fail.
plm(FileName, OptionList) :-
access(4, bimprolog),
% Handle options:
options(FileName, OptionList),
% Read input file:
see(FileName), read_clauses(CI), seen,
write('Finished reading '), write(FileName),nl,
name(FileName, NL),
name('.w', DOTW),
concat(NL, DOTW, OF),
name(OutFile, OF),
% Compile & write output file:
tell(OutFile),
cputime(Start),
compileallprocs(CI),
cputime(Stop), Time is Stop-Start,
told,
write('Total cputime is '),write(Time),nl,
fail.
plm(FileName, OptionList) :-
access(4, quintusprolog),
% Handle options:
options(FileName, OptionList),
% Read input file:
see(FileName), read_clauses(CI), seen,
write('Finished reading '), write(FileName),nl,
name(FileName, NL),
name('.w', DOTW),
concat(NL, DOTW, OF),
name(OutFile, OF),
% Compile & write output file:
statistics,
tell(OutFile),
compileallprocs(CI),
told,
statistics,
fail.
% Clean up all heap space used.
plm(_, _).
% Add options to data base:
options(FileName, OptionList) :-
set(2,[]),
atom(FileName),full_list(OptionList), add_options(OptionList), !.
options(FileName, OptionList) :-
write('First param is name of source file (atom)'),nl,
write('Second param is one option or a list of options (ground terms)'),
nl,abort, !.
compile_options(X) :- access(2,OptionList), member(X, OptionList), !.
add_options([Opt|OptionList]) :-
nonvar(Opt), !,
access(2,Options),
set(2,[Opt|Options]),
add_options(OptionList).
add_options([]).
read_clauses(ClauseInfo) :-
access(4, cprolog),
c_read_clauses(ClauseInfo), !.
read_clauses(ClauseInfo) :-
access(4, quintusprolog),
c_read_clauses(ClauseInfo), !.
read_clauses(ClauseInfo) :-
access(4, bimprolog),
b_read_clauses(ClauseInfo), !.
c_read_clauses(ClauseInfo) :- !,
read(Clause),
(Clause=end_of_file -> ClauseInfo=[];
getname(Clause, NameAr),
ClauseInfo=[source(NameAr,Clause)|Rest],
c_read_clauses(Rest)), !.
b_read_clauses(ClauseInfo) :-
read(Clause),
getname(Clause, NameAr),
ClauseInfo=[source(NameAr,Clause)|Rest],
b_read_clauses(Rest), !.
b_read_clauses([]).
getname(Clause, Name/Arity) :- !,
(Clause=(Head:-Body); Clause=Head),
Head=..[Name|Args],
my_length(Args, Arity), !.
% Generate and write code for all procedures in ClauseInfo:
compileallprocs([]) :-
alloc_option,
list_option, !.
compileallprocs(ClauseInfo) :-
filteroneproc(ClauseInfo, NextCI, NameAr, OneProc),
eliminate_disjunctions(OneProc,NewProc,NewClauses,Link),
Link = NextCI,
gc(compileproc(NameAr, NewProc, Code-[])),
write_plm(NameAr, Code),
compileallprocs(NewClauses), !.
% Take care of old-new allocate option:
alloc_option :-
compile_options(a),
not(compile_options(s)),
write_plm(allocate_dummy/0, [proceed]), !.
alloc_option.
% Procedure's end:
list_option :- compile_options(l), !.
list_option :- write(end), nl, nl, !.
filteroneproc([], [], _, []) :- !.
filteroneproc([source(NameAr,C)|Rest], NextCI, NameAr, [C|OneProc]) :-
filteroneproc(Rest, NextCI, NameAr, OneProc), !.
filteroneproc([source(N,C)|Rest], [source(N,C)|NextCI], NameAr, OneProc) :-
filteroneproc(Rest, NextCI, NameAr, OneProc), !.